ComputeNetRadiation Subroutine

private subroutine ComputeNetRadiation(cfc, alb, short, hum, temp, netRad)

Compute net radiation

References:

Wales-Smith, B. G. (1980). Estimates of net radiation for evaporation calculations, Hydrological Sciences Journal, 25:3, 237-242, DOI: 10.1080/02626668009491931

Arguments

Type IntentOptional Attributes Name
real(kind=float), intent(in) :: cfc

cloudiness factor complement

real(kind=float), intent(in) :: alb

albedo

real(kind=float), intent(in) :: short

shortwave radiation (W/m2)

real(kind=float), intent(in) :: hum

air relative hunidity (0-100)

real(kind=float), intent(in) :: temp

air temperature (degree celsius)

real(kind=float), intent(out) :: netRad

net radiation


Variables

Type Visibility Attributes Name Initial
real(kind=float), public :: albedotemp

temporary albedo value

real(kind=float), public :: cf

cloudiness factor

real(kind=float), public :: ea

actual vapor pressure (Pa)

real(kind=float), public :: es

saturation vapor pressure (Pa)

real(kind=float), public :: hum01

air relative humidity (0-1)

real(kind=float), public :: humMin

minimum value for air relative humidity (0-100)

real(kind=float), public :: netLong

net longwave radiation (W/m2)

real(kind=float), public :: netShort

net shortwave radiation (W/m2)


Source Code

SUBROUTINE ComputeNetRadiation &
!
(cfc, alb, short, hum, temp, netRad)

    
IMPLICIT NONE

!Arguments with intent(in):
REAL (KIND = float), INTENT(in) :: cfc !!cloudiness factor complement 
REAL (KIND = float), INTENT(in) :: alb !!albedo
REAL (KIND = float), INTENT(in) :: short !!shortwave radiation (W/m2)
REAL (KIND = float), INTENT(in) :: hum !! air relative hunidity (0-100)
REAL (KIND = float), INTENT(in) :: temp !! air temperature (degree celsius)

!Arguments with intent(out):
REAL (KIND = float), INTENT(out) :: netRad !!net radiation


!local declarations:
REAL (KIND = float) :: cf !!cloudiness factor
REAL (KIND = float) :: netShort !!net shortwave radiation (W/m2)
REAL (KIND = float) :: netLong !!net longwave radiation (W/m2)
REAL (KIND = float) :: albedotemp !!temporary albedo value
REAL (KIND = float) :: hum01 !!air relative humidity (0-1)
REAL (KIND = float) :: humMin !!minimum value for air relative humidity (0-100)
REAL (KIND = float) :: es !! saturation vapor pressure (Pa)
REAL (KIND = float) :: ea !!actual vapor pressure (Pa)
!------------------------------------end of declarations-----------------------

!cloudiness factor
cf = 1. - cfc

!net shortwave radiation
IF ( alb < 0. ) THEN
	albedotemp = 0.2
	netShort = (1. - albedotemp) * short
ELSE
	netShort = ( 1. - alb ) * short
END IF

!vapor pressure
humMin = 10
IF ( hum > humMin ) THEN
    hum01 = hum / 100.
ELSE
    hum01 = humMin / 100.
END IF

es = 6.107 * exp ( ( 17.27 * temp ) / ( temp + 237.3 ) )
ea = hum01 * es

!net longwave radiation ( Wales-Smith, 1980)

netLong = - ( stefanBoltzman * (temp + 273.15 )**4. ) * &
           ( 0.56 - 0.079 * ea**0.5 ) * ( 0.1 + 0.9 * cf )
	
!total net radiation
netRad = netShort + netLong

RETURN
END SUBROUTINE ComputeNetRadiation